home *** CD-ROM | disk | FTP | other *** search
/ Cream of the Crop 26 / Cream of the Crop 26.iso / os2 / octa209s.zip / octave-2.09 / libcruft / lapack / zgetf2.f < prev    next >
Text File  |  1996-07-19  |  4KB  |  137 lines

  1.       SUBROUTINE ZGETF2( M, N, A, LDA, IPIV, INFO )
  2. *
  3. *  -- LAPACK routine (version 2.0) --
  4. *     Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
  5. *     Courant Institute, Argonne National Lab, and Rice University
  6. *     September 30, 1994
  7. *
  8. *     .. Scalar Arguments ..
  9.       INTEGER            INFO, LDA, M, N
  10. *     ..
  11. *     .. Array Arguments ..
  12.       INTEGER            IPIV( * )
  13.       COMPLEX*16         A( LDA, * )
  14. *     ..
  15. *
  16. *  Purpose
  17. *  =======
  18. *
  19. *  ZGETF2 computes an LU factorization of a general m-by-n matrix A
  20. *  using partial pivoting with row interchanges.
  21. *
  22. *  The factorization has the form
  23. *     A = P * L * U
  24. *  where P is a permutation matrix, L is lower triangular with unit
  25. *  diagonal elements (lower trapezoidal if m > n), and U is upper
  26. *  triangular (upper trapezoidal if m < n).
  27. *
  28. *  This is the right-looking Level 2 BLAS version of the algorithm.
  29. *
  30. *  Arguments
  31. *  =========
  32. *
  33. *  M       (input) INTEGER
  34. *          The number of rows of the matrix A.  M >= 0.
  35. *
  36. *  N       (input) INTEGER
  37. *          The number of columns of the matrix A.  N >= 0.
  38. *
  39. *  A       (input/output) COMPLEX*16 array, dimension (LDA,N)
  40. *          On entry, the m by n matrix to be factored.
  41. *          On exit, the factors L and U from the factorization
  42. *          A = P*L*U; the unit diagonal elements of L are not stored.
  43. *
  44. *  LDA     (input) INTEGER
  45. *          The leading dimension of the array A.  LDA >= max(1,M).
  46. *
  47. *  IPIV    (output) INTEGER array, dimension (min(M,N))
  48. *          The pivot indices; for 1 <= i <= min(M,N), row i of the
  49. *          matrix was interchanged with row IPIV(i).
  50. *
  51. *  INFO    (output) INTEGER
  52. *          = 0: successful exit
  53. *          < 0: if INFO = -k, the k-th argument had an illegal value
  54. *          > 0: if INFO = k, U(k,k) is exactly zero. The factorization
  55. *               has been completed, but the factor U is exactly
  56. *               singular, and division by zero will occur if it is used
  57. *               to solve a system of equations.
  58. *
  59. *  =====================================================================
  60. *
  61. *     .. Parameters ..
  62.       COMPLEX*16         ONE, ZERO
  63.       PARAMETER          ( ONE = ( 1.0D+0, 0.0D+0 ),
  64.      $                   ZERO = ( 0.0D+0, 0.0D+0 ) )
  65. *     ..
  66. *     .. Local Scalars ..
  67.       INTEGER            J, JP
  68. *     ..
  69. *     .. External Functions ..
  70.       INTEGER            IZAMAX
  71.       EXTERNAL           IZAMAX
  72. *     ..
  73. *     .. External Subroutines ..
  74.       EXTERNAL           XERBLA, ZGERU, ZSCAL, ZSWAP
  75. *     ..
  76. *     .. Intrinsic Functions ..
  77.       INTRINSIC          MAX, MIN
  78. *     ..
  79. *     .. Executable Statements ..
  80. *
  81. *     Test the input parameters.
  82. *
  83.       INFO = 0
  84.       IF( M.LT.0 ) THEN
  85.          INFO = -1
  86.       ELSE IF( N.LT.0 ) THEN
  87.          INFO = -2
  88.       ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
  89.          INFO = -4
  90.       END IF
  91.       IF( INFO.NE.0 ) THEN
  92.          CALL XERBLA( 'ZGETF2', -INFO )
  93.          RETURN
  94.       END IF
  95. *
  96. *     Quick return if possible
  97. *
  98.       IF( M.EQ.0 .OR. N.EQ.0 )
  99.      $   RETURN
  100. *
  101.       DO 10 J = 1, MIN( M, N )
  102. *
  103. *        Find pivot and test for singularity.
  104. *
  105.          JP = J - 1 + IZAMAX( M-J+1, A( J, J ), 1 )
  106.          IPIV( J ) = JP
  107.          IF( A( JP, J ).NE.ZERO ) THEN
  108. *
  109. *           Apply the interchange to columns 1:N.
  110. *
  111.             IF( JP.NE.J )
  112.      $         CALL ZSWAP( N, A( J, 1 ), LDA, A( JP, 1 ), LDA )
  113. *
  114. *           Compute elements J+1:M of J-th column.
  115. *
  116.             IF( J.LT.M )
  117.      $         CALL ZSCAL( M-J, ONE / A( J, J ), A( J+1, J ), 1 )
  118. *
  119.          ELSE IF( INFO.EQ.0 ) THEN
  120. *
  121.             INFO = J
  122.          END IF
  123. *
  124.          IF( J.LT.MIN( M, N ) ) THEN
  125. *
  126. *           Update trailing submatrix.
  127. *
  128.             CALL ZGERU( M-J, N-J, -ONE, A( J+1, J ), 1, A( J, J+1 ),
  129.      $                  LDA, A( J+1, J+1 ), LDA )
  130.          END IF
  131.    10 CONTINUE
  132.       RETURN
  133. *
  134. *     End of ZGETF2
  135. *
  136.       END
  137.